home *** CD-ROM | disk | FTP | other *** search
/ Cream of the Crop 26 / Cream of the Crop 26.iso / os2 / octa209s.zip / octave-2.09 / libcruft / lapack / zungtr.f < prev    next >
Text File  |  1997-06-25  |  5KB  |  165 lines

  1.       SUBROUTINE ZUNGTR( UPLO, N, A, LDA, TAU, WORK, LWORK, INFO )
  2. *
  3. *  -- LAPACK routine (version 2.0) --
  4. *     Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
  5. *     Courant Institute, Argonne National Lab, and Rice University
  6. *     September 30, 1994
  7. *
  8. *     .. Scalar Arguments ..
  9.       CHARACTER          UPLO
  10.       INTEGER            INFO, LDA, LWORK, N
  11. *     ..
  12. *     .. Array Arguments ..
  13.       COMPLEX*16         A( LDA, * ), TAU( * ), WORK( LWORK )
  14. *     ..
  15. *
  16. *  Purpose
  17. *  =======
  18. *
  19. *  ZUNGTR generates a complex unitary matrix Q which is defined as the
  20. *  product of n-1 elementary reflectors of order N, as returned by
  21. *  ZHETRD:
  22. *
  23. *  if UPLO = 'U', Q = H(n-1) . . . H(2) H(1),
  24. *
  25. *  if UPLO = 'L', Q = H(1) H(2) . . . H(n-1).
  26. *
  27. *  Arguments
  28. *  =========
  29. *
  30. *  UPLO    (input) CHARACTER*1
  31. *          = 'U': Upper triangle of A contains elementary reflectors
  32. *                 from ZHETRD;
  33. *          = 'L': Lower triangle of A contains elementary reflectors
  34. *                 from ZHETRD.
  35. *
  36. *  N       (input) INTEGER
  37. *          The order of the matrix Q. N >= 0.
  38. *
  39. *  A       (input/output) COMPLEX*16 array, dimension (LDA,N)
  40. *          On entry, the vectors which define the elementary reflectors,
  41. *          as returned by ZHETRD.
  42. *          On exit, the N-by-N unitary matrix Q.
  43. *
  44. *  LDA     (input) INTEGER
  45. *          The leading dimension of the array A. LDA >= N.
  46. *
  47. *  TAU     (input) COMPLEX*16 array, dimension (N-1)
  48. *          TAU(i) must contain the scalar factor of the elementary
  49. *          reflector H(i), as returned by ZHETRD.
  50. *
  51. *  WORK    (workspace/output) COMPLEX*16 array, dimension (LWORK)
  52. *          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
  53. *
  54. *  LWORK   (input) INTEGER
  55. *          The dimension of the array WORK. LWORK >= N-1.
  56. *          For optimum performance LWORK >= (N-1)*NB, where NB is
  57. *          the optimal blocksize.
  58. *
  59. *  INFO    (output) INTEGER
  60. *          = 0:  successful exit
  61. *          < 0:  if INFO = -i, the i-th argument had an illegal value
  62. *
  63. *  =====================================================================
  64. *
  65. *     .. Parameters ..
  66.       COMPLEX*16         ZERO, ONE
  67.       PARAMETER          ( ZERO = ( 0.0D+0, 0.0D+0 ),
  68.      $                   ONE = ( 1.0D+0, 0.0D+0 ) )
  69. *     ..
  70. *     .. Local Scalars ..
  71.       LOGICAL            UPPER
  72.       INTEGER            I, IINFO, J
  73. *     ..
  74. *     .. External Functions ..
  75.       LOGICAL            LSAME
  76.       EXTERNAL           LSAME
  77. *     ..
  78. *     .. External Subroutines ..
  79.       EXTERNAL           XERBLA, ZUNGQL, ZUNGQR
  80. *     ..
  81. *     .. Intrinsic Functions ..
  82.       INTRINSIC          MAX
  83. *     ..
  84. *     .. Executable Statements ..
  85. *
  86. *     Test the input arguments
  87. *
  88.       INFO = 0
  89.       UPPER = LSAME( UPLO, 'U' )
  90.       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
  91.          INFO = -1
  92.       ELSE IF( N.LT.0 ) THEN
  93.          INFO = -2
  94.       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
  95.          INFO = -4
  96.       ELSE IF( LWORK.LT.MAX( 1, N-1 ) ) THEN
  97.          INFO = -7
  98.       END IF
  99.       IF( INFO.NE.0 ) THEN
  100.          CALL XERBLA( 'ZUNGTR', -INFO )
  101.          RETURN
  102.       END IF
  103. *
  104. *     Quick return if possible
  105. *
  106.       IF( N.EQ.0 ) THEN
  107.          WORK( 1 ) = 1
  108.          RETURN
  109.       END IF
  110. *
  111.       IF( UPPER ) THEN
  112. *
  113. *        Q was determined by a call to ZHETRD with UPLO = 'U'
  114. *
  115. *        Shift the vectors which define the elementary reflectors one
  116. *        column to the left, and set the last row and column of Q to
  117. *        those of the unit matrix
  118. *
  119.          DO 20 J = 1, N - 1
  120.             DO 10 I = 1, J - 1
  121.                A( I, J ) = A( I, J+1 )
  122.    10       CONTINUE
  123.             A( N, J ) = ZERO
  124.    20    CONTINUE
  125.          DO 30 I = 1, N - 1
  126.             A( I, N ) = ZERO
  127.    30    CONTINUE
  128.          A( N, N ) = ONE
  129. *
  130. *        Generate Q(1:n-1,1:n-1)
  131. *
  132.          CALL ZUNGQL( N-1, N-1, N-1, A, LDA, TAU, WORK, LWORK, IINFO )
  133. *
  134.       ELSE
  135. *
  136. *        Q was determined by a call to ZHETRD with UPLO = 'L'.
  137. *
  138. *        Shift the vectors which define the elementary reflectors one
  139. *        column to the right, and set the first row and column of Q to
  140. *        those of the unit matrix
  141. *
  142.          DO 50 J = N, 2, -1
  143.             A( 1, J ) = ZERO
  144.             DO 40 I = J + 1, N
  145.                A( I, J ) = A( I, J-1 )
  146.    40       CONTINUE
  147.    50    CONTINUE
  148.          A( 1, 1 ) = ONE
  149.          DO 60 I = 2, N
  150.             A( I, 1 ) = ZERO
  151.    60    CONTINUE
  152.          IF( N.GT.1 ) THEN
  153. *
  154. *           Generate Q(2:n,2:n)
  155. *
  156.             CALL ZUNGQR( N-1, N-1, N-1, A( 2, 2 ), LDA, TAU, WORK,
  157.      $                   LWORK, IINFO )
  158.          END IF
  159.       END IF
  160.       RETURN
  161. *
  162. *     End of ZUNGTR
  163. *
  164.       END
  165.